LongestFlowLength Function

public function LongestFlowLength(fdir, x, y) result(lmax)

compute longest flow length (m)

Arguments

Type IntentOptional Attributes Name
type(grid_integer), intent(in) :: fdir
real(kind=float), intent(in) :: x
real(kind=float), intent(in) :: y

Return Value real(kind=float)


Variables

Type Visibility Attributes Name Initial
type(grid_integer), public :: basin
integer(kind=short), public :: col

current cell

integer(kind=short), public :: i
integer(kind=short), public :: iDown

downstream cell

integer(kind=short), public :: j
integer(kind=short), public :: jDown

downstream cell

real(kind=float), public :: length
logical, public :: outlet
integer(kind=short), public :: row

current cell

real(kind=float), public :: xd
real(kind=float), public :: xu
real(kind=float), public :: yd
real(kind=float), public :: yu

Source Code

FUNCTION LongestFlowLength &
!
(fdir, x, y) &
!
RESULT (lmax)

IMPLICIT NONE

!Arguments with intent (in)
TYPE(grid_integer),INTENT(IN) :: fdir
REAL (KIND = float), INTENT(in) :: x, y  

!local declarations
REAL (KIND = float) :: lmax
REAL (KIND = float) :: length
REAL (KIND = float) :: xu, yu, xd, yd
TYPE(grid_integer) :: basin
INTEGER (KIND = short) :: row, col !!current cell
INTEGER (KIND = short) :: iDown, jDown !!downstream cell
INTEGER (KIND = short) :: i, j
LOGICAL :: outlet

!------------------------------end of declaration -----------------------------

!delineate river basin
CALL BasinDelineate (fdir, x, y, basin)

!overlay flow direction map
CALL GridResample (fdir, basin)


point1 % system = basin % grid_mapping
point2 % system = basin % grid_mapping
lmax = 0.
!loop trough basin
DO j = 1,basin % jdim
  DO i = 1,basin % idim
    IF (basin % mat (i,j) /= basin % nodata) THEN
        
        IF(CellIsSpring(i,j,basin)) THEN !found a spring
             
              length = 0.
       
              !follow the reach till basin outlet
               row                = i
               col                = j
               outlet             = .FALSE.
              
           DO WHILE (.NOT. outlet) ! follow the reach till the basin outlet 
    	                                                            
              CALL DownstreamCell(row, col, basin%mat(row,col), iDown, jDown)                         
              
              CALL GetXY (row,col,basin,xu,yu)
              CALL GetXY (iDown,jDown,basin,xd,yd)
              point1 % northing = yu  
              point1 % easting = xu
              point2 % northing = yd  
              point2 % easting = xd

              length = length + Distance(point1,point2)
              
              outlet = CheckOutlet(row,col,iDown,jDown,basin)
              IF (outlet) THEN
                 IF (length > lmax) THEN
                    lmax = length
                 END IF
              END IF
              
              !loop
              row = iDown
              col = jDown

           END DO
                      
        ENDIF
    END IF
  ENDDO
ENDDO 


RETURN
END FUNCTION LongestFlowLength